home *** CD-ROM | disk | FTP | other *** search
- *******************************************************************************
- *
- * fakeModalDialog and other supporting access routines and such.
- * Version 3.0
- *
- * Copyright (c)
- * Apple Computer, Inc. 1989-1990
- * All Rights Reserved.
- *
- * Written by Eric Soldan.
- *
- * Developer Technical Support Apple II Sample Code
- *
- * The purpose of this code is to handle dialogs in a variety of ways
- * that are more robust than what the toolbox offers. It also supports
- * the new movable/modeless dialog types described in the latest human
- * interface guidelines.
- *
- * See FMD.USAGE for usage information.
- *
- *******************************************************************************
-
-
- case on
-
- mcopy macros/FMD.Macros
-
- copy 2/ainclude/e16.types
- copy 2/ainclude/e16.control
- copy 2/ainclude/e16.event
- copy 2/ainclude/e16.lineedit
- copy 2/ainclude/e16.window
-
- longi on
- longa on
-
- ***********************************************************************
-
- fmdNoScrapForLE gequ $0001
- fmdMenuSelect gequ $0002
- fmdMenuKey gequ $0004
- fmdIBeam gequ $0008
- fmdDeskAcc gequ $0010
- fmdUpdateAll gequ $4000
- fmdMovable gequ $8000
-
- fakeModalDialog Start
-
- DefineStack
-
- dlgwptr long ;Must be at 1,s
- keepPort long ;Must be at 5,s
- ctlHndl long
- ctlPtr long
- theHndl long
- thePtr long
- whichWindow long
- tempwptr long
- code word
- editTask word
- yloc word
- xloc word
- wkind word
- menunum word
- zero word
-
- sizeFMDLocals EndLocals
-
- saveDPage word
- returnAddr block 3
-
- BegParms
- flags word ;bit 0 = 0, involve scrap for
- * ; lineEdit items.
- * ;bit 0 = 1, don't involve scrap for
- * ; lineEdit items.
- * ;bit 1 = 0, don't do _MenuSelect for
- * ; movable/modal dialogs.
- * ;bit 1 = 1, do _MenuSelect for
- * ; movable/modal dialogs.
- * ;bit 2 = 0, don't do _MenuKey for
- * ; movable/modal dialogs.
- * ;bit 2 = 1, do _MenuKey for
- * ; movable/modal dialogs.
- * ;bit 3 = 0, use arrow cursor
- * ; everywhere.
- * ;bit 3 = 1, use i-beam cursor for
- * ; lineEdit & textEdit ctls.
- * ;bit 4 = 0, let app handle desk
- * ; accessories.
- * ;bit 4 = 1, automatically handle desk
- * ; accessories.
- * ;bit 14 = 0, Don't update other
- * ; application windows.
- * ;bit 14 = 1, Update all windows.
- * ;bit 15 = 0, Modal window.
- * ;bit 15 = 1, movable/modal window.
- beepProc long ;Null, SysBeep. Negative, do nothing.
- eventHook long ;Optional -- pass a NULL for none.
- updateProc long ;Optional -- pass a NULL for default.
- event long ;Must be extended 5.0 event rec ptr.
- sizeFMDParms Endparms
-
- retval long ;Control ID hit. NULL if none.
- * ;If bit 31 is on, then retval
- * ;is a menu ID.
- ***
-
- FAKEMODALDIALOG entry
- phd ;Save directPage register.
- tsc ;Make space for locals.
- sec
- sbc #sizeFMDLocals
- tcs
- tcd ;Set directPage register.
-
- pla
- pla
- _GetPort ;Result space already there (keepPort).
-
- pha
- pha
- _FrontWindow ;Result space already there (dlgwptr).
-
- pha ;Find out if it is a DA window.
- pei dlgwptr+2
- pei dlgwptr
- _GetWKind
- pla
- sta wkind
- bpl gotit
-
- get1stRegWnd anop
- pha ;Result space for _GetWFrame.
-
- pha ;Result space for _GetNextWindow.
- pha
-
- pei dlgwptr+2
- pei dlgwptr
- _GetNextWindow
-
- lda 1,s ;Param for _GetWFrame.
- sta dlgwptr
- lda 3,s
- sta dlgwptr+2
-
- _GetWFrame
- pla
-
- and #fVis
- beq get1stRegWnd ;Window is invisible, so skip it.
-
- pha
- pei dlgwptr+2
- pei dlgwptr
- _GetWKind
- pla
- bmi get1stRegWnd ;Window is system window, so skip it.
-
- gotit stz retval ;Assume nothing interesting is
- stz retval+2 ;going to happen.
- stz code
- stz editTask ;For cut/copy/paste/clear signal.
- stz zero ;For optimization purposes.
-
- lda updateProc+1 ;Set up the update procedure for all
- bne FMDTemp1 ;cases. This also sets it up so that
- * ;TaskMaster can handle this window
- * ;from other parts of the application.
-
- lda #fmdStdDrawProc|-16
- sta updateProc+2
- lda #fmdStdDrawProc
- sta updateProc ;Use the default update procedure.
- FMDTemp1 anop
- pei updateProc+2
- pei updateProc
- pei dlgwptr+2
- pei dlgwptr
- _SetContentDraw ;Let the window and TaskMaster know.
-
- FMDTemp2 anop
- pha ;Make sure that top window is
- pha ;the active window.
- _GetPort
- pla
- sta keepPort
- pla
- sta keepPort+2
- pei dlgwptr+2
- pei dlgwptr
- _SetPort
-
- lda flags
- and #fmdIBeam
- beq FMDTemp3 ;No cursor changes.
-
- lda wkind
- bmi FMDTemp3
-
- pha ;Result space for control part.
-
- ldy #0 ;Point to where to put the handle.
- phy
- tdc
- clc
- adc #ctlHndl
- pha ;Pointer to ctlHndl now on stack.
-
- phy
- adc #yloc-ctlHndl
- pha ;Pointer to yloc now on stack.
- _GetMouse
-
- pei xloc ;Now that they are right, pass 'em on.
- pei yloc
- pei dlgwptr+2
- pei dlgwptr
- jsl fmdFindCursorCtl ;Find which control cursor is over.
- pla ;The part code, which we don't care
- * ;about here.
-
- beq arrowCursor ;Not over any control -- use arrow.
-
- jsr getCtlProc ;Find out what kind of control it is.
- cmp #editTextControl|-16
- beq ibeamCursor ;It is a TextEdit ctl, kind of
- * ;See fmdFindCursorCtl for more info.
- cmp #editLineControl|-16
- beq ibeamCursor ;It is a LineEdit tool.
-
- arrowCursor anop
- jsr ibeamTest
- bcc FMDTemp3
- _InitCursor
- bra FMDTemp3 ;We have an arrow cursor.
-
- ibeamCursor anop
- jsr ibeamTest
- bcs FMDTemp3 ;We have an ibeam cursor.
- jsl fmdIBeamCursor
-
- FMDTemp3 anop
- _SystemTask
-
- lda flags ;See if cut/copy/paste is tied to menu.
- and #fmdMenuSelect+fmdMenuKey
- beq FMDTemp4 ;Isn't keyDownEvt or mouseDownEvt.
- jsl fmdEditMenu ;Update the edit menu.
-
- FMDTemp4 anop
- pha ;Get the event.
- pea $FFFF
- pei event+2
- pei event
- _GetNextEvent
- pla
- beq exit ;Event shouldn't be handled by app.
-
- ldy #owhat
- lda [event],y
- sta code
- bne gotEvent
-
- exit lda code ;See if code is 0. If it is, force a
- bne exit0 ;NULL event, so the cursor will flash
- ldy #owhat ;for lineedit items, etc.
- sta [event],y
- pha
- pea 1
- pha
- pha
- pei event+2
- pei event
- _SendEventToCtl
- pla
-
- exit0 pei keepPort+2
- pei keepPort
- _SetPort
- tsc ;Get rid of local variables.
- clc
- adc #sizeFMDLocals
- tcs
- pld ;Restore directPage register.
- lda 1,s ;Move return address.
- sta 1+sizeFMDParms,s
- lda 2,s
- sta 2+sizeFMDParms,s
- tsc ;Get rid of passed parameters.
- adc #sizeFMDParms
- tcs
- jml _fmdNoError
-
- gotEvent anop
- lda eventHook+1
- beq noEventHook ;Zero, no event massaging.
-
- pei event+2 ;Give the event hook something
- pei event ;to play with.
- phk ;Push where we want to return to.
- pea noEventHook-1
-
- pha ;Push the eventHook address and return
- phb ;to it.
- pla
- lda eventHook
- dec a
- pha
- rtl
-
- noEventHook anop
- ldy #owhat
- lda [event],y
- sta code
-
- jsr doMouseDown
- bcc exit
-
- jsr doMenuKey
- bcc exit ;The key was a menu key.
-
- jsr doCutCopyPaste
- bcc exit ;We did a cut, copy, or paste.
-
- jsr doActivate
- bcc exit ;We did an activate.
-
- jsr doUpdate
- bcc exit ;We did an update.
-
- pha
- lda #0
- pha
- pha
- pha
- pei event+2
- pei event
- _SendEventToCtl
- pla
- beq exit0
-
- ldy #owmTaskData2 ;Get the ctl hndl of affected ctl.
- lda [event],y
- sta ctlHndl ;Save this in ctlHndl.
- iny
- iny
- lda [event],y
- sta ctlHndl+2
- jsr setValues
- brl exit
-
- ***
-
- doCutCopyPaste anop
- lda editTask ;We already have a task,
- bne ATask ;so don't check keypress.
-
- lda code
- cmp #keyDownEvt
- beq akey
- cmp #autoKeyEvt
- beq akey
-
- CCPsecexit anop
- sec
- rts
-
- akey lda flags
- and #fmdMenuKey
- bne CCPsecexit
- ldy #omodifiers ;See if it is a cut/copy/paste command.
- lda [event],y
- and #controlKey+optionKey+appleKey
- cmp #appleKey
- bne CCPsecexit ;Wrong modifiers -- no go.
-
- ldy #omessage
- lda [event],y
- ora #$20 ;Lower-case it.
-
- ldx #251
- cmp #'x'
- beq GotEditTask
- inx
- cmp #'c'
- beq GotEditTask
- inx
- cmp #'v'
- sec
- bne CCPsecexit
- GotEditTask anop
- stx editTask ;We have a valid task now.
-
- ATask pha ;Find out what control we are talking
- pha ;about.
- _FindTargetCtl
- ply
- sty ctlHndl
- ply
- sty ctlHndl+2
- bcs CCPsecexit
-
- lda editTask ;251 thru 254 (cut/copy/paste/clear)
- stz editTask ;This is also a flag, so we need to set
- sec ;it back.
- sbc #251-4
- asl a ;Assume TextEdit.
- tax
- stz theHndl
- stz theHndl+2
-
- jsr getCtlProc ;Find out what tool it is.
- cmp #editTextControl|-16
- beq FMDTemp5 ;It is TextEdit, and the xreg is set up
- * ;for TextEdit.
-
- cmp #editLineControl|-16
- bne CCPsecexit ;Not a LineEdit tool, so there can be
- * ;no cut/copy/paste.
-
- ldy #octlData ;It is LineEdit.
- lda [ctlPtr],y
- sta theHndl
- iny
- iny
- lda [ctlPtr],y
- sta theHndl+2
- txa
- and #7
- tax ;LineEdit tool.
-
- FMDTemp5 anop
- pei theHndl+2 ;All the below routines will use this
- pei theHndl ;parameter eventually.
- jmp (theTask,x)
-
- theTask dc i'leCut, leCopy, lePaste, leClear'
- dc i'teCut, teCopy, tePaste, teClear'
-
- leCut _LECut ;Do the cut.
- leCut0 lda flags
- lsr a
- bcs CCPclcexit
- _ZeroScrap ;Then conditionally do the LEToScrap.
- pha ;Conditionally, because of the bug for
- _LEGetScrapLen ;zero-length scrap.
- pla
- beq CCPclcexit
- _LEToScrap
- CCPclcexit anop
- clc ; clc and exit for Cut/Copy/Paste
- rts
- CCPclcexitz anop
- pla ; z routine pulls two words first
- pla
- clc
- rts
-
- leCopy _LECopy ;Do the copy.
- bra leCut0
-
- lePaste lda flags
- lsr a
- bcs FMDTemp6
-
- pha ;Boy, are we good citizens, or what?
- pha
- pei zero
- _GetScrapSize
- plx
- ply
- bcs CCPclcexitz ;Give up and do nothing.
- tya
- bne CCPclcexitz ;Way too big, so give up.
- txa
- beq CCPclcexitz ;Too small, so give up.
- _LEFromScrap
- bcs CCPclcexitz ;Somebody wasn't pleased, so give up.
- FMDTemp6 anop
- _LEPaste
- clc
- rts
-
- leClear _LEDelete ;Do the clear.
- clc
- rts
-
- teCut ldy #$28+2
- lda [ctlPtr],y
- and #$0400
- beq teCut0
- pla
- pla
- bra teCut1
- teCut0 _TECut ;Do the cut.
- teCut1 clc
- rts
-
- teCopy _TECopy ;Do the copy.
- clc
- rts
-
- tePaste _TEPaste ;Do the paste.
- clc
- rts
-
- teClear _TEClear ;Do the clear.
- clc
- rts
-
- getCtlProc anop
- ldy #2 ;Find out what tool it is.
- lda [ctlHndl],y
- sta ctlPtr+2
- lda [ctlHndl]
- sta ctlPtr ;Handle now dereferenced.
- ldy #octlProc+2 ;Get hi-word of proc address.
- lda [ctlPtr],y
- rts
-
- ***
-
- doActivate anop
- lda code
- cmp #activateEvt
- beq FMDTemp7
- sec
- rts
-
- FMDTemp7 anop
- pha
- pha
- _GetPort
-
- pha ;Result space for _GetWControls.
- pha
- ldy #omessage+2 ;Find out which window we are
- lda [event],y ;talking about.
- tax
- dey
- dey
- lda [event],y
- phx
- pha
- phx
- pha
- _SetPort
-
- ldy #omodifiers ;See if we are activating.
- lda [event],y
- lsr a
- bcc noMenuProc ;We are not, so don't update menus.
-
- pha ;See if we have a proc to set the state
- pha ;of the menus.
- jsl fmdGetMenuProc
- plx ;Lo-word of address.
- pla ;Hi-word of address.
- bne haveMenuProc ;We have a menu Proc -- go do it.
- txy
- beq noMenuProc ;We don't have one.
-
- haveMenuProc anop
- phk ;Push where we want to return to.
- pea noMenuProc-1
- xba ;Push just the lo-byte as the hi-byte
- pha ;of ret addr.
- phb
- pla
- dex ;Push the lo-word minus 1 for rtl.
- phx
- rtl
-
- noMenuProc anop
- _GetWControls
- pla
- sta ctlHndl
- pla
- sta ctlHndl+2
-
- FMDLoop1 anop
- lda ctlHndl+1
- beq ActivateExit
- jsr getCtlProc
-
- ldx #nakend-nak-2
- naklook cmp >nak,x
- beq ActivateNextCtl
- dex
- dex
- bpl naklook
-
- cmp #editLineControl|-16
- bne ActivateInval ;Invalidate unless lineEdit.
- * ;Invalidate this one selectively. If
- * ;it is the window's target, then
- * ;invalidate it.
-
- ldy #octlMoreFlags
- lda [ctlPtr],y
- bpl ActivateNextCtl ;It doesn't need invalidating.
-
- ActivateInval lda ctlPtr ;Push pointer to bounding rect of ctl.
- clc
- adc #octlRect
- tax
- lda ctlPtr+2
- adc #0
- pha
- phx
- _InvalRect
- jsr getCtlProc ;An easy way to redereference.
-
- ActivateNextCtl anop
- ldy #2
- lda [ctlPtr]
- sta ctlHndl
- lda [ctlPtr],y
- sta ctlHndl+2
- bra FMDLoop1
-
- ActivateExit anop
- _SetPort
- clc ;displayed in the correct state.
- rts
-
- nak dc i'$8100,$8900,$8D00' ;These don't need invalidating ever.
- nakend anop
-
- ***
-
- doUpdate anop
- lda code
- cmp #updateEvt
- beq FMDTemp8
- sec
- rts ;Event isn't an update event.
-
- noUpdate anop
- stz code ;We don't do this update, since the
- clc ;window that needs to be updated isn't
- rts ;the modal dialog.
-
- FMDTemp8 anop
- ldy #omessage+2 ;Find out which window we are
- lda [event],y ;talking about.
- sta tempwptr+2
- tax
- dey
- dey
- lda [event],y
- sta tempwptr
- tay
-
- lda flags
- and #fmdUpdateAll
- bne realUpdate ;We are movable/modal, so update it,
- * ;whatever it is.
-
- cpy dlgwptr
- bne noUpdate ;We are modal, so don't update other
- cpx dlgwptr+2 ;windows.
- bne noUpdate ;We are modal, so don't update other
- * ;windows.
-
- realUpdate anop
- phx ;Result space for _GetContentDraw.
- phy
- phx ;For _GetContentDraw
- phy
- _GetContentDraw
- plx
- pla
- bne haveProc
- txy
- beq UpdateExit
-
- haveProc anop
- phk ;Push return address for updateProc.
- pea UpdateRetLoc-1
-
- xba ;Push just the lo-byte as the hi-byte
- pha ;of ret addr.
- phb
- pla
-
- dex ;Push the lo-word minus 1 for rtl.
- phx
-
- pei tempwptr+2
- pei tempwptr
- _BeginUpdate
-
- rtl ;Go to the updateProc.
-
- UpdateRetLoc anop
- pei tempwptr+2
- pei tempwptr
- _EndUpdate
-
- UpdateExit anop
- clc
- rts
-
- ***
-
- doMouseDown anop
- lda code
- cmp #mouseDownEvt
- beq FMDTemp9
- sec
- rts
-
- FMDTemp9 anop
- pha ;Find out what window we clicked on.
- pei zero
- tdc
- clc
- adc #whichWindow
- pha
- ldy #owhere+2
- lda [event],y
- sta xloc
- pha
- dey
- dey
- lda [event],y
- sta yloc
- pha
- _FindWindow
- pla
- bpl FMDTemp9a
-
- tax ;Keep it for _SystemClick's use.
- lda flags
- and #fmdDeskAcc
- beq MDtoBeep
-
- pei event+2 ;Let the DA have some fun, too.
- pei event
- pei whichWindow+2
- pei whichWindow
- phx
- _SystemClick
- clc
- rts
-
- FMDTemp9a anop
- cmp #wInDrag
- bne FMDTemp10
-
- jsr isMyWindow ;See if "whichWindow" equals dlgwptr.
- bcc MDtoBeep ;Wrong window -- nice try, though.
-
- lda flags
- bpl FMDTemp9z ;MDnoBeep
-
- ldy #0 ;Drag resolution -- default.
- phy
- pei xloc ;Starting mouse location.
- pei yloc
- pea 8 ;TaskMaster uses this value, so we do.
- phy ;Default cursor boundary.
- phy
- pei dlgwptr+2
- pei dlgwptr
- _DragWindow
- ldy #omodifiers
- lda [event],y
- and #appleKey
- bne FMDTemp9z
- pei dlgwptr+2
- pei dlgwptr
- _SelectWindow
- FMDTemp9z anop
- brl MDnoBeep
-
- FMDTemp10 anop
- cmp #wInMenuBar
- bne FMDTemp11 ;Not in menu bar.
- lda flags
- lsr a
- lsr a
- bcc MDtoBeep ;_MenuSelect not allowed -- go do beep.
- lda flags
- and #fmdMenuSelect+fmdMenuKey
- beq MDtoBeep ;Modal dialog, no menus allowed, so go
- * ;do beep.
- brl doMenuTask ;Movable/modal dialog, so go
- * ;handle menu bar.
-
- FMDTemp11 anop
- cmp #wInFrame ;Don't beep if on dialog frame. This
- beq FMDTemp12 ;branch is the most efficient sizewise,
- * ;since we won't hit any controls.
- cmp #wInContent
- bne MDtoBeep ;We didn't click in a content.
-
- FMDTemp12 anop
- jsr isMyWindow
- bcs FMDTemp13
- MDtoBeep anop
- brl MDBeep
-
- FMDTemp13 anop
- pha
- pha
- _FrontWindow
- pei dlgwptr+2
- pei dlgwptr
- _SelectWindow
-
- pla
- plx
- cmp whichWindow
- bne MDnoBeep
- cpx whichWindow+2
- bne MDnoBeep
-
- FMDTemp14 anop
- pha
- pei zero
- tdc
- clc
- adc #ctlHndl
- pha
- pei xloc
- pei yloc
- pei dlgwptr+2
- pei dlgwptr
- _FindControl
- pla
- beq MDnoBeep ;Missed all of the controls.
-
- jsr fixLEflash
-
- pha
- pei xloc
- pei yloc
- lda #-1
- pha
- pha
- pei ctlHndl+2
- pei ctlHndl
- _TrackControl
- pla
- sta >ctlPart
- beq MDnoBeep
-
- ldy #owmTaskData2 ;Put the found control in TaskData2
- lda ctlHndl ;for application.
- sta [event],y
- iny
- iny
- lda ctlHndl+2
- sta [event],y
- jsr setValues
- clc
- rts
-
- MDBeep lda beepProc+2
- bmi MDnoBeep ;Negative, do nothing.
- ora beepProc
- beq MDSysBeep ;Zero, regular SysBeep.
-
- pei event+2 ;Give the custom "beep" something
- pei event ;to play with.
- phk ;Push where we want to return to.
- pea MDnoBeep-1
- lda beepProc+1 ;Push updateProc addr and return to it.
- pha
- phb
- pla
- lda beepProc
- dec a
- pha
- rtl
- MDSysBeep anop
- _SysBeep
- MDnoBeep anop
- clc
- rts
-
- fixLEflash anop
- jsr getCtlProc
- cmp #editLineControl|-16
- bne FixLErts
- ldy #octlMoreFlags
- lda [ctlPtr],y
- bmi FixLErts ;LineEdit control already target.
-
- ldy #octlData ;For lineEdit controls that are
- lda [ctlPtr],y ;inactive, make sure that there is no
- sta theHndl ;text currently selected. If there is,
- iny ;TrackControl will temporarily flash
- iny ;the selected range. So, we check to
- lda [ctlPtr],y ;see if we are a lineEdit control. If
- sta theHndl+2 ;we are, we see if we are active. If
- ldy #2 ;we aren't, we set selEnd to be the
- lda [theHndl] ;same as selStart. Simple, huh?
- sta thePtr
- lda [theHndl],y
- sta thePtr+2
-
- ldy #oleSelStart ;thePtr is deref'ed lineEdit record.
- lda [thePtr],y ;Set selEnd to be the same as selStart.
- iny
- iny
- sta [thePtr],y ;It is done. It is good. The end.
-
- FixLErts anop
- rts
-
- ***
-
- fmdGetCtlPart entry
- FMDGETCTLPART entry
- lda >ctlPart
- sta 4,s
- jml _fmdNoError
- ctlPart dc i'0'
-
- ***
-
- setValues anop
- pha ;Convert the control handle into an ID
- pha ;for application.
- pei ctlHndl+2
- pei ctlHndl
- _GetCtlID
- pla
- ply
- bcs FMDTemp15 ;List controls have non-super-control
- * ;scrollbars. We therefore don't want
- * ;to return a control-id here, since
- * ;non-super-controls don't have an id to
- * ;return anyway. (We get an error $1007
- * ;if it isn't a super-control, so we
- * ;don't want to return anything
- * ;anything, since it garbage.)
- sta retval
- sty retval+2 ;Return the ctlID in retval.
-
- FMDTemp15 anop
- jsr getCtlProc ;See if radio button or checkbox.
- cmp #radioControl|-16
- beq radioButtonHit
- cmp #checkControl|-16
- bne SetValuesRts
-
- CheckBoxHit anop
- pha
- pei ctlHndl+2
- pei ctlHndl
- _GetCtlValue
- pla
- beq FMDTemp16 ;Do a true NOT.
- lda #$FFFF
- FMDTemp16 anop
- inc a
- FMDTemp17 anop
- pha
- pei ctlHndl+2
- pei ctlHndl
- _SetCtlValue
- SetValuesRts anop
- rts
-
- radioButtonHit anop
- lda #1
- bra FMDTemp17
-
- doMenuTask anop
- clc
- doMenuTaskz anop
- php ;Keep carry status.
- pei event+2
- pei event
- lda #0
- pha
- pha
- bcs FMDTemp19
- jsr ibeamTest
- bcc FMDTemp18
- _InitCursor ;This only gets done if it is currently
- * ;an ibeam.
- FMDTemp18 anop
- _MenuSelect ;Handle the pullDown.
- bra FMDTemp20
- FMDTemp19 anop
- _MenuKey ;Handle the menu key.
-
- FMDTemp20 anop
- plp ;Restore carry status.
- ldy #owmTaskData
- lda [event],y
- beq MenuTaskRts ;PullDown, cclear. MenuKey, cset.
- tax
- iny
- iny
- lda [event],y
- sta menunum
-
- cpx #250 ;See if we should open a DA.
- bcs FMDTemp21
-
- lda flags ;See if we should handle DA's.
- and #fmdDeskAcc
- beq FMDTemp23 ;No, hilite menu to normal.
- phx ;Open the can-o-worms.
- phx
- _InitCursor
- _OpenNDA
- pla
- bra FMDTemp23 ;Do _HiliteMenu and leave.
-
- FMDTemp21 anop
- cpx #256 ;Anything above close, let app do it.
- bcs FMDTemp24 ;Not an undo/cut/copy/paste/clear/close
- * ;menu item.
-
- ldy wkind
- bpl FMDTemp22
-
- cpx #255
- beq CloseNDA ;Go let the DA handle it.
-
- txa
- sec
- sbc #249
- pha
- pha
- _SystemEdit
- pla
- bra FMDTemp23 ;Do _HiliteMenu and leave.
-
- FMDTemp22 anop
- cpx #255
- beq FMDTemp24 ;Let app do close for non DA windows.
- cpx #250
- beq FMDTemp24 ;Let app do undo also.
-
- stx editTask ;Let cut/copy/paste know what to do.
- jsr doCutCopyPaste
-
- FMDTemp23 anop
- pei zero
- pei menunum
- _HiliteMenu
- clc
- rts
-
- FMDTemp24 anop
- stx retval ;Low-order word contains the ID # of
- ora #$8000 ;item selected. Hi-order word contains
- sta retval+2 ;the menu ID # with hi-bit turned on.
- clc ;The hi-bit is to allow the application
- * ;to distinguish this from a control ID.
- * ;This means ID's must be hi-bit off!!
- MenuTaskRts rts
-
- CloseNDA anop
- pha
- pha
- _FrontWindow
- lda 1,s ;Be extra paranoid -- it helps.
- cmp keepPort ;Make sure that the desk accessory was
- bne FMDTemp21b ;not active port when fakeModalDialog
- lda 3,s ;was called. If it is, we will get
- cmp keepPort+2 ;into trouble closing it, because we
- bne FMDTemp21b ;will do a SetPort to keepPort when we
- lda dlgwptr ;leave. So, if keepPort is the port we
- sta keepPort ;are about to close, change it to the
- lda dlgwptr+2 ;dlgwptr (the app's dialog window).
- sta keepPort+2
- FMDTemp21b anop
- _CloseNDAByWinPtr
- bra FMDTemp23
-
- isMyWindow anop
- lda whichWindow
- cmp dlgwptr
- bne NotMyWindow
- lda whichWindow+2
- cmp dlgwptr+2
- beq YesMyWindow
- NotMyWindow anop
- clc
- YesMyWindow anop
- rts
-
- ***
-
- doMenuKey anop
- lda code
- cmp #keyDownEvt
- beq FMDTemp22a
- sec
- MenuKeyRts anop
- rts ;It isn't a menu key, since it isn't
- * ;even a key.
-
- FMDTemp22a anop
- lda flags
- and #fmdMenuKey
- sec
- beq MenuKeyRts ;Menu keys not allowed (carry is set).
-
- brl doMenuTaskz ;Carry still set, which is important.
-
- ***
-
- ibeamTest anop
- lda wkind
- clc
- bmi IBeamRts ;Don't do our ibeam when a DA is up.
- pha ;This is so we know what cursor we
- pha ;currently have. Otherwise, we will be
- _GetCursorAdr ;setting the cursor a lot, and it will
- pha ;flash.
- pha
- jsl fmdGetIBeamAdr ;This clears carry (no error returned.)
- pla
- ply
- eor 1,s
- bne NoIBeam ;Carry is clear.
- tya
- eor 3,s
- bne NoIBeam ;Carry is clear.
- sec
- NoIBeam pla
- pla
- IBeamRts anop
- rts ;Carry set means we now have ibeam.
-
- End
-
-
- *******************************************************************************
- *******************************************************************************
- *******************************************************************************
-
- * From this point are additional entry points and useful access routines.
-
- ********************
-
- fmdStdDrawProc Start
-
- FMDSTDDRAWPROC entry
- pha ;What kind of window frame do we want?
- pha
- pha
- _GetPort
- _GetWFrame
- pla ;fAlert is bit 13. fFlex is bit 9.
- asl a
- asl a ;fAlert is now in bit 15.
- bmi StdNoFrame ;We already have a frame, and
- * ;it looks maaahvelous!
-
- and #$0800 ;Bit 9 moved into bit 11.
- bne StdNoFrame
-
- pha
- _GetMasterSCB
- pla
- xba
- asl a
- lda #5
- bcs in640
- lsr a
- in640 pha ;Keep the width for _InsetRect.
- pha ;Push the width for _FrameRect.
- pea 2
- _SetPenSize
- plx ;The width for _InsetRect.
- lda #StdworkRect
- ldy #StdworkRect|-16
- phy ;Push parameters for _FrameRect.
- pha
- phy ;Push parameters for _InsetRect.
- pha
- phx ;Push the width for _InsetRect.
- pea 2
- phy ;Push parameters for _GetPortRect.
- pha
- _GetPortRect
- _InsetRect
- _FrameRect
- _PenNormal
-
- StdNoFrame anop
- pha
- pha
- _GetPort
- _DrawControls
- rtl
-
- StdworkRect ds 8
-
- End
-
- ********************
-
- fmdSetMenuProc Start
-
- FMDSETMENUPROC entry
- lda 4,s
- sta >menuProc
- lda 6,s
- sta >menuProc+2
- lda 1,s
- sta 5,s
- lda 2,s
- sta 6,s
- pla
- pla
- exit jml _fmdNoError
-
- fmdGetMenuProc entry
- FMDGETMENUPROC entry
- lda >menuProc
- sta 4,s
- lda >menuProc+2
- sta 6,s
- bra exit
-
- menuProc dc i4'0'
-
- End
-
- ********************
-
- fmdEditMenu Start
-
- DefineStack
-
- selStart long
- selEnd long
- leHndl long
- lePtr long
- ctlPtr long ;Must be 2nd from end of local space.
- ctlHndl long ;Must be at end of local space.
-
- sizeEditLocals EndLocals
-
- saveDPage word
- returnAddr block 3
-
- ***
-
- FMDEDITMENU entry
- phd ;Save directPage register.
-
- tsc ;Make space for locals, part 1.
- sec
- sbc #sizeEditLocals
- tcd
-
- pha ;Find out if it is a DA window.
- pha
- pha
- _FrontWindow
- _GetWKind
- pla
- bpl FMDTemp23 ;It is a regular window.
- pea 250
- _EnableMItem ;Enable undo.
- pea 255
- _EnableMItem ;Enable close.
- ldx #%1111 ;Enable cut/copy/paste/clear.
- brl EMSetMenus
-
- FMDTemp23 anop
- pha
- pha
- _FindTargetCtl
- bcc FMDTemp23a ;There is a target, so go do some work.
- brl EMnoTool
-
- FMDTemp23a anop
- ldy #2 ;Deref target ctl handle into ctlPtr.
- lda [ctlHndl],y
- pha
- lda [ctlHndl]
- pha
-
- tdc ;Make space for locals, part 2.
- tcs ;Stack ptr & directPage ptr agree now.
-
- ldy #octlProc+2 ;Get hi-word of Proc address.
- lda [ctlPtr],y
-
-
- cmp #editTextControl|-16
- beq EMTextEdit ;It is TextEdit tool.
- cmp #editLineControl|-16
- bne EMnoTool ;Not LineEdit tool.
-
- EMLineEdit anop
- ldy #octlData ;Get the lineEdit handle from
- lda [ctlPtr],y ;the control's data field.
- sta leHndl
- iny
- iny
- lda [ctlPtr],y
- sta leHndl+2
-
- ldy #2 ;Dereference leHndl.
- lda [leHndl]
- sta lePtr
- lda [leHndl],y
- sta lePtr+2
-
- ldx #0
- jsr canWePaste
-
- ldy #oleSelStart
- lda [lePtr],y
- iny
- iny
- cmp [lePtr],y
- beq EMSetMenus
- txa
- ora #%1011 ;Enable cut/copy/clear.
- tax
- bra EMSetMenus
-
- EMTextEdit anop
- ldy #0
- phy
- tdc
- clc
- adc #selStart
- pha
- phy
- adc #selEnd-selStart
- pha
- pei ctlHndl+2
- pei ctlHndl
- _TEGetSelection
- ldx #%1011
- lda selStart
- cmp selEnd
- bne EMhasSelect
- lda selStart+2
- cmp selEnd+2
- bne EMhasSelect
- ldx #0
-
- EMhasSelect anop
- jsr canWePaste
-
- ldy #$28+2 ;Find out if we are read-only.
- lda [ctlPtr],y
- and #$0400 ;Bit 26, please.
- beq EMSetMenus
-
- txa ;Don't allow cut & paste.
- and #2
- tax
- bra EMSetMenus
-
- EMnoTool anop
- ldx #0 ;Bit 0 for cut, 1 for copy,
- * ;2 for paste.
- EMSetMenus anop
- txa
- ldy #251
- jsr setOneMenu
- jsr setOneMenu
- jsr setOneMenu
- jsr setOneMenu
-
- EMExit tdc ;Remove local space.
- clc
- adc #sizeEditLocals
- tcs
- pld ;Restore directPage register.
- jml _fmdNoError
-
- setOneMenu anop
- lsr a
- pha
- phy
- phy
- bcs SetEnable
- SetDisable anop
- _DisableMItem
- bra FMDTemp24
- SetEnable anop
- _EnableMItem
- FMDTemp24 anop
- ply
- iny
- pla
- rts
-
- canWePaste anop
- txa ;Assume no paste.
- and #$FFFF-4
- pha
-
- pha ;See if paste should be available.
- pha
- pea 0
- _GetScrapSize
- plx
- ply
-
- pla ;Get cut/copy/paste status back.
-
- bcs PasteExit ;Error, so no paste.
- phy
- ply
- bne YesWeCanPaste
- txy
- beq PasteExit
- YesWeCanPaste anop
- ora #4
-
- PasteExit anop
- tax
- rts
-
- End
-
- ********************
-
- fmdFindCursorCtl Start
-
- DefineStack
-
- hndl long ;Must be at 1,s
- ctlHndl long
- ctlPtr long
-
- sizeCursorLocals EndLocals
-
- saveDPage word
- returnAddr block 3
-
- BegParms
- wptr long
- yloc word
- xloc word
- ctlHndlPtr long ;Where to store the control handle.
- sizeCursorParms Endparms
-
- ctlPart word
-
- ***
-
- FMDFINDCURSORCTL entry
- phd ;Save directPage register.
- tsc ;Make space for locals.
- sec
- sbc #sizeCursorLocals
- tcs
- tcd ;Set directPage register.
-
- pei wptr+2
- pei wptr
- _GetWControls ;Result space already there (hndl).
-
- stz ctlPart ;Assume failure.
- stz ctlHndl
- stz ctlHndl+2
-
- FMDLoop2 anop
- lda hndl+1
- beq FindCursorExit ;No more controls to check.
-
- ldy #2 ;Deref hndl.
- lda [hndl]
- sta ctlPtr
- lda [hndl],y
- sta ctlPtr+2
-
- pha ;Result space for _PtInRect
- pea 0 ;Push pointer to point.
- tdc
- clc
- adc #yloc
- pha
- lda ctlPtr ;Push ptr to bounding rect of ctl.
- clc
- adc #octlRect
- tax
- lda ctlPtr+2
- adc #0
- pha
- phx
- _PtInRect
- pla
- beq FindCursorNextCtl
-
- sta ctlPart
- lda hndl ;Copy the temp hndl to the "real" one.
- sta ctlHndl
- lda hndl+2
- sta ctlHndl+2
-
- ldy #octlProc+2 ;Get hi-word of Proc address.
- lda [ctlPtr],y
- cmp #editTextControl|-16
- bne FindCursorExit
-
- FindCursorNextCtl anop
- ldy #2
- lda [ctlPtr] ;Get the next control handle.
- sta hndl
- lda [ctlPtr],y
- sta hndl+2
- bra FMDLoop2
-
- FindCursorExit anop
- lda ctlHndl ;Return the ctl hndl (could be NULL).
- sta [ctlHndlPtr]
- lda ctlHndl+2
- ldy #2
- sta [ctlHndlPtr],y
-
- tsc ;Get rid of local variables.
- clc
- adc #sizeCursorLocals
- tcs
- pld ;Restore directPage register.
- lda 1,s ;Move return address.
- sta 1+sizeCursorParms,s
- lda 2,s
- sta 2+sizeCursorParms,s
- tsc ;Get rid of passed parameters.
- adc #sizeCursorParms
- tcs
- jml _fmdNoError
-
- End
-
- ********************
-
- * Here are some useful routines for control information access via a ctl ID.
-
- ********************
-
- * This routine takes a window pointer, a lineEdit control ID, and a pointer to
- * a pascal string. It stuffs the pascal string into the lineEdit control.
- * It also select the full range of the text. This is useful because the
- * target control should have all the text selected when a dialog comes up.
- * Doing it here means you don't have to do it elsewhere.
-
- fmdLESetText Start
-
- DefineStack
-
- ctlHndl long
- ctlPtr long
- leHndl long
- lePtr long
- lineHndl long
- linePtr long
- cstr long
- lineLength word
- rect block 8 ;Must be > oleViewRect ($10)
-
- sizeLESetLocals EndLocals
-
- saveDPage word
- returnAddr block 3
-
- BegParms
- pstr long ;Pointer to string space.
- lineEditID long ;ID of lineEdit control.
- wptr long ;Window that owns the control.
- sizeLESetParms Endparms
-
- ***
-
- FMDLESETTEXT entry
- jsr lineEditSetup ;Set up everything we need.
- bcs exit ;Couldn't dereference for some reason.
-
- pei cstr+2 ;Set text to c-string.
- pei cstr
- lda [pstr] ;Get length of pascal string.
- and #$FF
- pha
- pei leHndl+2
- pei leHndl
- _LESetText
- bcs exit
-
- pha ;Invalidate view rect of lineEdit.
- pha
- _GetPort ;Save the current port.
- pei wptr+2
- pei wptr
- _SetPort ;Make the window the current port
- * ;(for _InvalRect).
-
- jsr lineEditDeref ;Redereference -- slow but small.
- ldy #oleSelStart
- lda #0
- pha ;Hi-word for _InvalRect.
- sta [lePtr],y
- iny
- iny ;Point at leSelEnd.
- lda [pstr] ;Get length of pascal string.
- and #$FF
- sta [lePtr],y
-
- ldy #oleViewRect+6 ;Copy lineEdit viewRect into rect.
- FMDTemp25 anop
- lda [lePtr],y
- tyx
- sta <rect-oleViewRect,x
- dey
- dey
- cpy #oleViewRect
- bcs FMDTemp25
-
- tdc ;Hi-word alreay on stack. (It's a 0).
- adc #rect ;Carry still clear.
- pha
- _InvalRect ;Inval that rect.
-
- _SetPort ;Put the port back.
-
- exitNoErr anop
- lda #0 ;Return no error.
- exit tay ;Save error code.
-
- tdc ;Get rid of local variables.
- clc
- adc #sizeLESetLocals
- tcs
- pld ;Restore directPage register.
-
- lda 1,s ;Move return address.
- sta 1+sizeLESetParms,s
- lda 2,s
- sta 2+sizeLESetParms,s
-
- tsc ;Pull passed parms off stack.
- adc #sizeLESetParms
- tcs
-
- tya ;Recover error code.
- jml _fmdSetError
-
- ***
-
- fmdLEGetText entry
- FMDLEGETTEXT entry
- jsr lineEditSetup ;Set up everything we need.
- bcs exit ;Couldn't dereference for some reason.
-
- pei linePtr+2 ;Copy the text into the string.
- pei linePtr
- pei cstr+2
- pei cstr
- pea 0
- pei lineLength
- _BlockMove
-
- ldy lineLength ;Store the p-string length and also
- tya ;terminate the string for the c dudes.
- shortm ;Use 8-bit accumulator.
- sta [pstr] ;Save the p-string length byte.
- lda #0
- sta [cstr],y ;Terminate the c-string.
- longm ;Set accumulator back to 16-bit.
-
- bra exitNoErr ;Return no error.
-
- ***
-
- lineEditSetup anop
- plx ;Save return address so stack frame
- * ;setup works.
-
- phd ;Save directPage register.
- tsc ;Make space for locals.
- sec
- sbc #sizeLESetLocals
- tcs
- tcd ;Set directPage register.
-
- phx ;Put return address back.
-
- lda pstr ;Also point past p-string length
- ldx pstr+2 ;for c-strings.
- inc a
- bne FMDTemp26
- inx
- FMDTemp26 anop
- sta cstr
- stx cstr+2
-
- pha ;Get the control handle via wptr,id.
- pha
- pei wptr+2
- pei wptr
- pei lineEditID+2
- pei lineEditID
- _GetCtlHandleFromID
- plx
- stx ctlHndl
- plx
- stx ctlHndl+2
- bcs rts1
-
- ldy #2 ;Dereference ctlHndl.
- lda [ctlHndl]
- sta ctlPtr
- lda [ctlHndl],y
- sta ctlPtr+2
-
- ldy #octlData ;Get the lineEdit handle from
- lda [ctlPtr],y ;the control's data field.
- sta leHndl
- iny
- iny
- lda [ctlPtr],y
- sta leHndl+2
-
- lineEditDeref anop
- ldy #2 ;Dereference leHndl.
- lda [leHndl]
- sta lePtr
- lda [leHndl],y
- sta lePtr+2
-
- ldy #oleLength
- lda [lePtr],y
- sta lineLength
-
- ldy #oleLineHandle
- lda [lePtr],y
- sta lineHndl
- iny
- iny
- lda [lePtr],y
- sta lineHndl+2
-
- ldy #2 ;Dereference lineHndl.
- lda [lineHndl]
- sta linePtr
- lda [lineHndl],y
- sta linePtr+2
- clc ;Everything worked.
-
- rts1 rts
-
- End
-
- ********************
-
- fmdWhichRadio Start
-
- DefineStack
-
- ctlHndl long ;Must be at 1,s
- ctlPtr long
- ctlID long ;ID of some radio button control.
- theRadBut word
- notHere word ;Flag for active button not found.
-
- sizeWRLocals EndLocals
-
- saveDPage word
- returnAddr block 3
-
- BegParms
- famNum word
- wptr long ;Window that owns the control.
- sizeWRParms Endparms
-
- radioNum word
-
- ***
-
- FMDWHICHRADIO entry
- phd ;Save directPage register.
- tsc ;Make space for locals.
- sec
- sbc #sizeWRLocals
- tcs
- tcd ;Set directPage register.
-
- lda #$FFFF ;This is supposed to be a bogus value
- sta radioNum ;(0 is legit).
- sta notHere ;Assume we won't find active radio
- sta ctlID+2 ;button of correct family number.
-
- pei wptr+2
- pei wptr
- _GetWControls ;Result space already there (ctlHndl).
- bcs WhichRadioExit
-
- FMDLoop3 anop
- lda ctlHndl+1 ;See if we have a NULL handle yet.
- beq FMDEndLoop3
-
- jsr WRDerefCtl ;Deref ctlHndl into ctlPtr.
-
- ldy #octlProc+2 ;Get hi-word of Proc address.
- lda [ctlPtr],y
- cmp #radioControl|-16
- bne WRNextCtl ;Not a radio button. Skip it.
-
- ldy #octlFlag
- lda [ctlPtr],y
- and #$7F
- cmp famNum ;See if it is "our" family.
- bne WRNextCtl ;Not related.
-
- ldy #octlID+2 ;See if this is the smallest ctlID for
- lda [ctlPtr],y ;our family yet.
- tax
- dey
- dey
- lda [ctlPtr],y
- cpx ctlID+2
- bcc wrSmaller
- bne wrNotSmall ;It isn't.
- cmp ctlID
- bcs wrNotSmall ;It isn't.
- wrSmaller anop ;It is, so remember it.
- sta ctlID
- stx ctlID+2
-
- wrNotSmall anop
- tax
- ldy #octlValue
- lda [ctlPtr],y
- beq WRNextCtl ;This isn't the active radio button.
- stx theRadBut ;This is the one, so remember enough
- stz notHere ;of it.
-
- WRNextCtl anop
- ldy #2
- lda [ctlPtr]
- sta ctlHndl
- lda [ctlPtr],y
- sta ctlHndl+2
- bra FMDLoop3
-
- FMDEndLoop3 anop
- lda notHere
- bmi wrFail
- lda theRadBut
- sec
- sbc ctlID
- wrFail sta radioNum ;This is what the programmer was
- * ;yearning for.
-
- lda #0 ;Return no error.
-
- WhichRadioExit anop
- tay ;Save error code.
-
- tdc ;Get rid of local variables.
- clc
- adc #sizeWRLocals
- tcs
- pld ;Restore directPage register.
-
- lda 1,s ;Move return address.
- sta 1+sizeWRParms,s
- lda 2,s
- sta 2+sizeWRParms,s
-
- tsc ;Pull passed parms off stack.
- adc #sizeWRParms
- tcs
-
- tya ;Recover error code.
- jml _fmdSetError
-
- WRDerefCtl anop
- ldy #2
- lda [ctlHndl]
- sta ctlPtr
- lda [ctlHndl],y
- sta ctlPtr+2
- rts
-
- End
-
- ********************
-
- fmdIBeamCursor Start
-
- FMDIBEAMCURSOR entry
- lda >curIBeam+2 ;Change the cursor to current ibeam.
- pha
- lda >curIBeam
- pha
- _SetCursor
- bra exit
-
- fmdInitIBeam entry
- FMDINITIBEAM entry
- lda #ibeamCursor ;Make default ibeam current ibeam.
- sta >curIBeam
- lda #ibeamCursor|-16
- sta >curIBeam+2
- bra exit
-
- fmdGetIBeamAdr entry
- FMDGETIBEAMADR entry
- lda >curIBeam ;Return address of current ibeam.
- sta 4,s
- lda >curIBeam+2
- sta 6,s
- bra exit
-
- fmdSetIBeam entry
- FMDSETIBEAM entry
- lda 4,s ;Change the ibeam to alternate ibeam.
- sta >curIBeam
- lda 6,s
- sta >curIBeam+2
- lda 1,s
- sta 5,s
- lda 2,s
- sta 6,s
- pla
- pla
- exit jml _fmdNoError
-
- curIBeam dc i4'0'
- ibeamCursor dc i1'9,0,3,0'
- dc i1'$00,$F0,$F0,$00,$00,$00'
- dc i1'$00,$0F,$00,$00,$00,$00'
- dc i1'$00,$0F,$00,$00,$00,$00'
- dc i1'$00,$0F,$00,$00,$00,$00'
- dc i1'$00,$0F,$00,$00,$00,$00'
- dc i1'$00,$0F,$00,$00,$00,$00'
- dc i1'$00,$0F,$00,$00,$00,$00'
- dc i1'$00,$0F,$00,$00,$00,$00'
- dc i1'$00,$F0,$F0,$00,$00,$00'
- *
- dc i1'$00,$00,$00,$00,$00,$00'
- dc i1'$00,$00,$00,$00,$00,$00'
- dc i1'$00,$00,$00,$00,$00,$00'
- dc i1'$00,$00,$00,$00,$00,$00'
- dc i1'$00,$00,$00,$00,$00,$00'
- dc i1'$00,$00,$00,$00,$00,$00'
- dc i1'$00,$00,$00,$00,$00,$00'
- dc i1'$00,$00,$00,$00,$00,$00'
- dc i1'$00,$00,$00,$00,$00,$00'
- dc i1'4,0,6,0'
-
- End
-
- ********************
-
- fmdStartUp Start
-
- FMDSTARTUP entry
- lda #0
- pha
- pha
- jsl fmdSetMenuProc
- jml fmdInitIBeam
-
- End
-
- ********************
-
- fmdShutDown Start
-
- FMDSHUTDOWN entry
- jml _fmdNoError
-
- End
-
- ********************
-
- _fmdNoError Start
-
- lda #0
-
- _fmdSetError entry
- sta >fmdErr
- bra exit
-
- fmdGetError entry
- lda >fmdErr
- sta 4,s
- exit cmp #1
- rtl
-
- fmdErr dc i'0'
-
- End
-
- ********************
-